home *** CD-ROM | disk | FTP | other *** search
/ Cream of the Crop 26 / Cream of the Crop 26.iso / os2 / octa209s.zip / octave-2.09 / libcruft / lapack / zunghr.f < prev    next >
Text File  |  1996-07-19  |  4KB  |  146 lines

  1.       SUBROUTINE ZUNGHR( N, ILO, IHI, A, LDA, TAU, WORK, LWORK, INFO )
  2. *
  3. *  -- LAPACK routine (version 2.0) --
  4. *     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
  5. *     Courant Institute, Argonne National Lab, and Rice University
  6. *     September 30, 1994
  7. *
  8. *     .. Scalar Arguments ..
  9.       INTEGER            IHI, ILO, INFO, LDA, LWORK, N
  10. *     ..
  11. *     .. Array Arguments ..
  12.       COMPLEX*16         A( LDA, * ), TAU( * ), WORK( LWORK )
  13. *     ..
  14. *
  15. *  Purpose
  16. *  =======
  17. *
  18. *  ZUNGHR generates a complex unitary matrix Q which is defined as the
  19. *  product of IHI-ILO elementary reflectors of order N, as returned by
  20. *  ZGEHRD:
  21. *
  22. *  Q = H(ilo) H(ilo+1) . . . H(ihi-1).
  23. *
  24. *  Arguments
  25. *  =========
  26. *
  27. *  N       (input) INTEGER
  28. *          The order of the matrix Q. N >= 0.
  29. *
  30. *  ILO     (input) INTEGER
  31. *  IHI     (input) INTEGER
  32. *          ILO and IHI must have the same values as in the previous call
  33. *          of ZGEHRD. Q is equal to the unit matrix except in the
  34. *          submatrix Q(ilo+1:ihi,ilo+1:ihi).
  35. *          1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
  36. *
  37. *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
  38. *          On entry, the vectors which define the elementary reflectors,
  39. *          as returned by ZGEHRD.
  40. *          On exit, the N-by-N unitary matrix Q.
  41. *
  42. *  LDA     (input) INTEGER
  43. *          The leading dimension of the array A. LDA >= max(1,N).
  44. *
  45. *  TAU     (input) COMPLEX*16 array, dimension (N-1)
  46. *          TAU(i) must contain the scalar factor of the elementary
  47. *          reflector H(i), as returned by ZGEHRD.
  48. *
  49. *  WORK    (workspace/output) COMPLEX*16 array, dimension (LWORK)
  50. *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
  51. *
  52. *  LWORK   (input) INTEGER
  53. *          The dimension of the array WORK. LWORK >= IHI-ILO.
  54. *          For optimum performance LWORK >= (IHI-ILO)*NB, where NB is
  55. *          the optimal blocksize.
  56. *
  57. *  INFO    (output) INTEGER
  58. *          = 0:  successful exit
  59. *          < 0:  if INFO = -i, the i-th argument had an illegal value
  60. *
  61. *  =====================================================================
  62. *
  63. *     .. Parameters ..
  64.       COMPLEX*16         ZERO, ONE
  65.       PARAMETER          ( ZERO = ( 0.0D+0, 0.0D+0 ),
  66.      $                   ONE = ( 1.0D+0, 0.0D+0 ) )
  67. *     ..
  68. *     .. Local Scalars ..
  69.       INTEGER            I, IINFO, J, NH
  70. *     ..
  71. *     .. External Subroutines ..
  72.       EXTERNAL           XERBLA, ZUNGQR
  73. *     ..
  74. *     .. Intrinsic Functions ..
  75.       INTRINSIC          MAX, MIN
  76. *     ..
  77. *     .. Executable Statements ..
  78. *
  79. *     Test the input arguments
  80. *
  81.       INFO = 0
  82.       IF( N.LT.0 ) THEN
  83.          INFO = -1
  84.       ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, N ) ) THEN
  85.          INFO = -2
  86.       ELSE IF( IHI.LT.MIN( ILO, N ) .OR. IHI.GT.N ) THEN
  87.          INFO = -3
  88.       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  89.          INFO = -5
  90.       ELSE IF( LWORK.LT.MAX( 1, IHI-ILO ) ) THEN
  91.          INFO = -8
  92.       END IF
  93.       IF( INFO.NE.0 ) THEN
  94.          CALL XERBLA( 'ZUNGHR', -INFO )
  95.          RETURN
  96.       END IF
  97. *
  98. *     Quick return if possible
  99. *
  100.       IF( N.EQ.0 ) THEN
  101.          WORK( 1 ) = 1
  102.          RETURN
  103.       END IF
  104. *
  105. *     Shift the vectors which define the elementary reflectors one
  106. *     column to the right, and set the first ilo and the last n-ihi
  107. *     rows and columns to those of the unit matrix
  108. *
  109.       DO 40 J = IHI, ILO + 1, -1
  110.          DO 10 I = 1, J - 1
  111.             A( I, J ) = ZERO
  112.    10    CONTINUE
  113.          DO 20 I = J + 1, IHI
  114.             A( I, J ) = A( I, J-1 )
  115.    20    CONTINUE
  116.          DO 30 I = IHI + 1, N
  117.             A( I, J ) = ZERO
  118.    30    CONTINUE
  119.    40 CONTINUE
  120.       DO 60 J = 1, ILO
  121.          DO 50 I = 1, N
  122.             A( I, J ) = ZERO
  123.    50    CONTINUE
  124.          A( J, J ) = ONE
  125.    60 CONTINUE
  126.       DO 80 J = IHI + 1, N
  127.          DO 70 I = 1, N
  128.             A( I, J ) = ZERO
  129.    70    CONTINUE
  130.          A( J, J ) = ONE
  131.    80 CONTINUE
  132. *
  133.       NH = IHI - ILO
  134.       IF( NH.GT.0 ) THEN
  135. *
  136. *        Generate Q(ilo+1:ihi,ilo+1:ihi)
  137. *
  138.          CALL ZUNGQR( NH, NH, NH, A( ILO+1, ILO+1 ), LDA, TAU( ILO ),
  139.      $                WORK, LWORK, IINFO )
  140.       END IF
  141.       RETURN
  142. *
  143. *     End of ZUNGHR
  144. *
  145.       END
  146.